home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Language/OS - Multiplatform Resource Library
/
LANGUAGE OS.iso
/
smaltalk
/
manchest.lha
/
MANCHESTER
/
manchester
/
2.2
/
infinity.st
< prev
next >
Wrap
Text File
|
1993-07-24
|
6KB
|
201 lines
" NAME infinity
AUTHOR manchester
FUNCTION Provides a class of infinities
ST-VERSION 2.2
PREREQUISITES
CONFLICTS
DISTRIBUTION world
VERSION 1
DATE 22 Jan 1989
SUMMARY
This is a set of
changes that implements infinity in the Number hierarchy. I obtained the
original changes from the author of an article in comp.lang.smalltalk.
I have just installed it in my image and I have found two small omissions
which are corrected in what is below; there might be others. Arithmetic
between infinities is not defined but magnitude comparisons are implemented.
"
!Point methodsFor: 'testing'!
isFinite
^x isFinite and: [y isFinite]!
isInfinite
^x isInfinite or: [y isInfinite]! !
Number comment:
'The abstract class Number is at the top of the number hierarchy. Its subclasses are Float, Fraction, Integer and Infinity.'!
!Number methodsFor: 'mathematical functions'!
raisedTo: aNumber
"Answer the receiver raised to aNumber."
aNumber = 0 ifTrue: [^1]. "Special case of exponent=0"
aNumber = 1 ifTrue: [^self]. "Special case of exponent=1"
aNumber isInteger
ifTrue: ["Do the special case of integer power"
^self raisedToInteger: aNumber].
^(aNumber * self ln) exp "Otherwise raise it to the power using logarithms"! !
!Number methodsFor: 'testing'!
isFinite
^true!
isInfinite
^false! !
!Number methodsFor: 'coercing'!
retry: aSymbol coercing: aNumber
"Arithmetic represented by the symbol, aSymbol,
could not be performed with the receiver and the argument,
aNumber, because of the differences in representation. Coerce either the
receiver or the argument, depending on which has higher generality, and
try again. If the symbol is the equals sign, answer false if the argument is
not a Number. If the generalities are the same, create an error message."
(aSymbol == #= and: [(aNumber isKindOf: Number) == false])
ifTrue: [^false].
self generality < aNumber generality
ifTrue: [aNumber isInfinite
ifTrue: [^aNumber retryReverseOf: aSymbol with: self]
ifFalse: [^(aNumber coerce: self) perform: aSymbol with: aNumber]].
self generality > aNumber generality
ifTrue: [^self perform: aSymbol with: (self coerce: aNumber)].
self error: 'coercion attempt failed'! !
Number subclass: #Infinity
instanceVariableNames: 'positive '
classVariableNames: 'NegativeInfinity PositiveInfinity '
poolDictionaries: ''
category: 'Numeric-Numbers'!
Infinity comment:
'I have two instances representing positive and negative infinity.
Instance Variables :-
positive <Boolean> : if true the instance represents positive infinity. if false, negative infinity'!
!Infinity methodsFor: 'arithmetic'!
* aNumber
"Multiply the receiver by the argument and answer with the result."
aNumber isInfinite
ifTrue: [self errorUndefinedResult: #*]
ifFalse: [^self]!
+ aNumber
"Multiply the receiver by the argument and answer with the result."
(aNumber isInfinite and: [aNumber ~~ self])
ifTrue: [self errorUndefinedResult: #*]
ifFalse: [^self]!
- aNumber
"Multiply the receiver by the argument and answer with the result."
(aNumber isInfinite)
ifTrue: [self errorUndefinedResult: #*]
ifFalse: [^self]!
/ aNumber
"Multiply the receiver by the argument and answer with the result."
(aNumber isInfinite or: [aNumber = 0])
ifTrue: [self errorUndefinedResult: #/]
ifFalse: [^self]! !
!Infinity methodsFor: 'comparing'!
< aNumber
"Positive infinity is greater than any number than positive infinity. Analogously,
negative infinity is less than any other number other than negative infinity"
aNumber == self
ifTrue: [^false].
^positive not!
= aNumber
^aNumber == self!
hash
^self asOop! !
!Infinity methodsFor: 'testing'!
isFinite
^false!
isInfinite
^true! !
!Infinity methodsFor: 'coercing'!
generality
"Infinities are more general than scalars, but not more general than vectors (e.g. Points)"
^85!
retryReverseOf: aSymbol with: aNumber
(aSymbol == #* or: [aSymbol == #+])
ifTrue: [^self perform: aSymbol with: aNumber].
(aSymbol == #/ and: [aNumber isFinite])
ifTrue: [^0].
(aSymbol == #< and: [aNumber isFinite])
ifTrue: [^positive].
(aSymbol == #> and: [ aNumber isFinite ])
ifTrue: [^positive not].
(aSymbol == #= and: [ aNumber isFinite ])
ifTrue: [ ^false ].
self errorUndefinedResult: aSymbol! !
!Infinity methodsFor: 'printing'!
printOn: aStream
aStream
nextPutAll: self class name;
nextPutAll:
(positive
ifTrue: [' positive']
ifFalse: [' negative'])! !
!Infinity methodsFor: 'errors'!
errorUndefinedResult: messageName
self error: 'Undefined result in an Infinity ', messageName! !
!Infinity methodsFor: 'private'!
setPositive: aBoolean
positive _ aBoolean! !
Infinity class
instanceVariableNames: ''!
!Infinity class methodsFor: 'class initialization'!
initialize
"Infinity initialize"
PositiveInfinity _ self basicNew setPositive: true.
NegativeInfinity _ self basicNew setPositive: false! !
!Infinity class methodsFor: 'instance creation'!
negative
"Return the unique instance of negative infinity"
^NegativeInfinity!
new
self shouldNotImplement!
positive
"Return the unique instance of positive infinity"
^PositiveInfinity! !
Infinity initialize!